InitSpatialAverageSnow Subroutine

public subroutine InitSpatialAverageSnow(fileini, pathout, rain, swe, meltCoeff, freeWater, snowMelt)

Initialization of spatial average of snow variables

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(in) :: fileini
character(len=*), intent(in) :: pathout
type(grid_real), intent(in) :: rain

rainfall rate (m/s)

type(grid_real), intent(in) :: swe

snow water equivalent (m)

type(grid_real), intent(in) :: meltCoeff

snow melt coefficient (mm/day/C)

type(grid_real), intent(in) :: freeWater

water in snow pack (m)

type(grid_real), intent(in) :: snowMelt

snow melt i the time step (m)


Variables

Type Visibility Attributes Name Initial
type(IniList), public :: iniDB

Source Code

SUBROUTINE InitSpatialAverageSnow   & 
!
 (fileini, pathout, rain, swe, meltCoeff, freeWater, snowMelt )  

IMPLICIT NONE

!arguments with intent in:
CHARACTER(LEN = *), INTENT(IN)    :: fileini 
CHARACTER(LEN = *), INTENT(IN)    :: pathout     
TYPE (grid_real), INTENT(IN) :: rain !!rainfall rate (m/s)
TYPE (grid_real), INTENT(IN) :: swe !!snow water equivalent (m)
TYPE (grid_real), INTENT(IN) :: meltCoeff !!snow melt coefficient (mm/day/C)
TYPE (grid_real), INTENT(IN) :: freeWater !! water in snow pack (m)
TYPE (grid_real), INTENT(IN) :: snowMelt !!snow melt i the time step (m)

!local declarations
TYPE(IniList)          :: iniDB
!-------------------------------end of declaration-----------------------------

!  open and read configuration file
CALL IniOpen (fileini, iniDB) 

! search for active variable for output
CALL Catch ('info', 'SpatialAverage', 'checking for snow active variables ')

countsnow = 0

!rainfall (liquid precipitation)
IF ( IniReadInt ('rain', iniDB, section = 'snow') == 1) THEN
   IF ( .NOT. ALLOCATED (rain % mat) ) THEN
       CALL Catch ('warning', 'SpatialAverage', 'liquid precipitation not allocated, &
                                            forced to not export spatial average ')
       snowout (1) = .FALSE.
   ELSE
       snowout (1) = .TRUE.
       countsnow = countsnow + 1
   END IF
ELSE
   snowout (1) = .FALSE.
END IF

!snow water equivalent
IF ( IniReadInt ('snow-water-equivalent', iniDB, section = 'snow') == 1) THEN
   IF ( .NOT. ALLOCATED (swe % mat) ) THEN
       CALL Catch ('warning', 'SpatialAverage', 'swe not allocated, &
                                            forced to not export spatial average ')
       snowout (2) = .FALSE.
   ELSE
       snowout (2) = .TRUE.
       countsnow = countsnow + 1
   END IF
ELSE
   snowout (2) = .FALSE.
END IF

!snow melt coefficient
IF ( IniReadInt ('melt-coefficient', iniDB, section = 'snow') == 1) THEN
   IF ( .NOT. ALLOCATED (meltCoeff % mat) ) THEN
       CALL Catch ('warning', 'SpatialAverage', 'melt-coefficient not allocated, &
                                            forced to not export spatial average ')
       snowout (3) = .FALSE.
   ELSE
       snowout (3) = .TRUE.
       countsnow = countsnow + 1
   END IF
ELSE
   snowout (3) = .FALSE.
END IF


!snow covered area
IF ( IniReadInt ('snow-covered-area', iniDB, section = 'snow') == 1) THEN
   IF ( .NOT. ALLOCATED (swe % mat) ) THEN
       CALL Catch ('warning', 'SpatialAverage', 'snow water equivalent not allocated, &
                                            forced to not export snow covered area ')
       snowout (4) = .FALSE.
   ELSE
       snowout (4) = .TRUE.
       countsnow = countsnow + 1
   END IF
ELSE
   snowout (4) = .FALSE.
END IF

!liquid water in snowpack
IF ( IniReadInt ('water-in-snow', iniDB, section = 'snow') == 1) THEN
   IF ( .NOT. ALLOCATED (freeWater % mat) ) THEN
       CALL Catch ('warning', 'SpatialAverage', 'water-in-snow not allocated, &
                                            forced to not export spatial average ')
       snowout (5) = .FALSE.
   ELSE
       snowout (5) = .TRUE.
       countsnow = countsnow + 1
   END IF
ELSE
   snowout (5) = .FALSE.
END IF

!snow melt
IF ( IniReadInt ('snow-melt', iniDB, section = 'snow') == 1) THEN
   IF ( .NOT. ALLOCATED (snowMelt % mat) ) THEN
       CALL Catch ('warning', 'SpatialAverage', 'snow-melt not allocated, &
                                            forced to not export spatial average ')
       snowout (6) = .FALSE.
   ELSE
       snowout (6) = .TRUE.
       countsnow = countsnow + 1
   END IF
ELSE
   snowout (6) = .FALSE.
END IF


snowInitialized = .TRUE.

CALL IniClose (iniDB) 


CALL ConfigureExtents (fileini, pathout)


RETURN
END SUBROUTINE InitSpatialAverageSnow